home *** CD-ROM | disk | FTP | other *** search
-
- /* Copyright (C) 1988, 1989 Herve' Touati, Aquarius Project, UC Berkeley */
-
- foreign_file('random.o',[get_random,set_random]).
- foreign(get_random, c, get_random([-integer])).
- foreign(set_random, c, set_random(+integer)).
-
- init :- load_foreign_files(['random.o'], []),
- abolish(foreign_file, 2),
- abolish(foreign, 3).
-
- main :-
- set_random(23),
- make_list(20000,L),
- qsort(L,X,[]),
- write_limited(20,X), nl.
-
- qsort([X|L],R,R0) :-
- partition(L,X,L1,L2),
- qsort(L2,R1,R0),
- qsort(L1,R,[X|R1]).
- qsort([],R,R).
-
- partition([X|L],Y,[X|L1],L2) :-
- X<Y, !,
- partition(L,Y,L1,L2).
- partition([X|L],Y,L1,[X|L2]) :-
- partition(L,Y,L1,L2).
- partition([],_,[],[]).
-
- make_list(0,[]) :- !.
- make_list(N,[X|Xs]) :-
- get_random(X),
- N1 is N -1,
- make_list(N1,Xs).
-
- write_limited(N,X) :- write('['), write_limited2(N,X), write('...]'), nl.
- write_limited2(0,_) :- !.
- write_limited2(_,[]) :- !.
- write_limited2(N,[X|Xs]) :- N1 is N - 1,
- write(X), write(','),
- write_limited2(N1,Xs).
-